home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / smaltalk / gnu_st.lha / gnu_st / smalltalk-1.1.1 / Dictionary.st < prev    next >
Text File  |  1991-09-12  |  10KB  |  386 lines

  1. "======================================================================
  2. |
  3. |   Dictionary Method Definitions
  4. |
  5.  ======================================================================"
  6.  
  7.  
  8. "======================================================================
  9. |
  10. | Copyright (C) 1990, 1991 Free Software Foundation, Inc.
  11. | Written by Steve Byrne.
  12. |
  13. | This file is part of GNU Smalltalk.
  14. |
  15. | GNU Smalltalk is free software; you can redistribute it and/or modify it
  16. | under the terms of the GNU General Public License as published by the Free
  17. | Software Foundation; either version 1, or (at your option) any later version.
  18. | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
  19. | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
  20. | FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
  21. | details.
  22. | You should have received a copy of the GNU General Public License along with
  23. | GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
  24. | Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
  25. |
  26.  ======================================================================"
  27.  
  28.  
  29. "
  30. |     Change Log
  31. | ============================================================================
  32. | Author       Date       Change 
  33. | sbb         12 Sep 91      Added Dictionary class>>new so subclasses can win.
  34. |
  35. | sbyrne      6 May 90      Fixed grow method to preserve associations in use in
  36. |              the dictionary instead of making new ones.  This
  37. |              should be faster, and doesn't break compiled methods
  38. |              that reference global variables when Smalltalk grows.
  39. |
  40. | sbyrne     24 Apr 90      Fix at:ifAbsent: to deal with failure better (and be
  41. |              a tad more efficient).  Kudos (or BarNone's,
  42. |              depending on preference) to Andy Valencia.
  43. |
  44. | sbyrne      7 Apr 90      Modified at:put: to resuse the existing Association
  45. |              if there is one, rather than create a new one all the
  46. |              time.  This was causing lossage when setting global
  47. |              variables in Smalltalk that previous usages weren't
  48. |              being changed.
  49. |
  50. | sbyrne     25 Apr 89      created.
  51. |
  52. "
  53.  
  54. Set variableSubclass: #Dictionary
  55.     instanceVariableNames: ''
  56.     classVariableNames: ''
  57.     poolDictionaries: ''
  58.     category: nil.
  59.  
  60. Dictionary comment: 
  61. 'I implement a dictionary, which is an object that is indexed by
  62. unique objects (typcially instances of Symbol), and associates another
  63. object with that index.  I use the equality operator = to determine
  64. equality of indices.' !
  65.  
  66. "### The initblocks variable should not be globally visible, I think"
  67. "This is a HACK HACK HACK.  We want to reference the InitBlocks global variable
  68. from within some methods in System Dictionary.  However, after this file
  69. redefines at:put: from the built-in one, and until UndefinedObject.st is 
  70. loaded, defining isNil for nil, at:put: for dictionaries does not work
  71. properly.  So we do it here.  The basic problem is that InitBlocks should
  72. maybe be kept elsewhere, and not be globally visible."
  73. Smalltalk at: #InitBlocks put: nil!
  74.  
  75. !Dictionary class methodsFor: 'instance creation'!
  76.  
  77. new
  78.     "Builtins defines a #new method, so that during bootstrap there is a way
  79.      to create dictionaries.  Unfortunately, this #new method only creates
  80.      dictionaries, so subclasses when trying to use this method, lose big.
  81.      This fixes the problem."
  82.     ^self new: 32
  83. ! !
  84.  
  85.  
  86. !Dictionary methodsFor: 'accessing'!
  87. add: anAssociation
  88.     | index |
  89.     index _ self findKeyIndex: anAssociation key.
  90.     (self basicAt: index) isNil
  91.     ifTrue: [ tally _ tally + 1].
  92.     self basicAt: index put: anAssociation.
  93.     ^anAssociation
  94. !
  95.  
  96. at: key put: value
  97.     | index assoc |
  98.     index _ self findKeyIndex: key.
  99.     (assoc _ self basicAt: index) isNil
  100.     ifTrue: [ self basicAt: index
  101.                put: (Association key: key value: value).
  102.           tally _ tally + 1 ]
  103.     ifFalse: [ assoc value: value ].
  104.     ^value
  105. !
  106.  
  107. at: key
  108.     ^self at: key ifAbsent: [ ^self error: 'key not found' ]
  109. !
  110.  
  111. at: key ifAbsent: aBlock
  112.     | assoc |
  113.     assoc _ self basicAt: (self findKeyIndex: key).
  114.     assoc isNil
  115.             ifTrue: [ ^aBlock value ]
  116.             ifFalse: [ ^assoc value ]
  117. !
  118.     
  119. associationAt: key
  120.     ^self associationAt: key ifAbsent: [ ^self error: 'key not found' ]
  121. !
  122.  
  123. associationAt: key ifAbsent: aBlock
  124.     | index assoc|
  125.     index _ self findKeyIndex: key.
  126.     assoc _ self basicAt: index.
  127.     assoc isNil ifTrue: [ ^aBlock value ]
  128.                 ifFalse: [ ^assoc ]
  129. !
  130.  
  131. keyAtValue: value ifAbsent: exceptionBlock
  132.     self associationsDo:
  133.         [ :assoc | value = assoc value
  134.                  ifTrue: [ ^assoc key ] ].
  135.     ^exceptionBlock value
  136. !
  137.  
  138. keyAtValue: value
  139.     ^self keyAtValue: value ifAbsent: []
  140. !
  141.  
  142. keys
  143.     | aSet |
  144.     aSet _ Set new: tally.
  145.     self keysDo: [ :aKey | aSet add: aKey ].
  146.     ^aSet
  147. !
  148.  
  149. values
  150.     | aBag |
  151.     aBag _ Bag new.
  152.     self do: [ :aValue | aBag add: aValue ].
  153.     ^aBag
  154. !!
  155.  
  156.  
  157.  
  158. !Dictionary methodsFor: 'dictionary testing'!
  159.  
  160. includesAssociation: anAssociation
  161.     | assoc |
  162.     assoc _ self associationAt: anAssociation key ifAbsent: [ ^false ].
  163.     ^assoc value = anAssociation value
  164. !
  165.  
  166. includesKey: key
  167.     self associationAt: key ifAbsent: [ ^false ].
  168.     ^true
  169. !
  170.  
  171. includes: anObject
  172.     self do: [ :element | element = anObject ifTrue: [ ^true ] ].
  173.     ^false
  174. !
  175.  
  176. occurrencesOf: aValue
  177.     | count |
  178.     count _ 0.
  179.     self do: [ :element | element = aValue
  180.                     ifTrue: [ count _ count + 1] ].
  181.     ^count
  182. !!
  183.  
  184.  
  185.  
  186. !Dictionary methodsFor: 'dictionary removing'!
  187.  
  188. removeAssociation: anAssociation
  189.     "### does this check the value as well as the key?"
  190.     self removeKey: anAssociation key ifAbsent: [].
  191.     ^anAssociation
  192. !
  193.  
  194. removeKey: key
  195.     ^self removeKey: key ifAbsent: [ ^self error: 'key not found' ]
  196. !
  197.  
  198. removeKey: key ifAbsent: aBlock
  199.     | index assoc |
  200.     index _ self findKeyIndexNoGrow: key ifAbsent: [ ^aBlock value ].
  201.     assoc _ self basicAt: index.
  202.     self basicAt: index put: nil.
  203.     tally _ tally - 1.
  204.     self rehashObjectsAfter: index.
  205.     ^assoc value
  206. !
  207.  
  208. remove: anObject
  209.     self error: 'remove: not allowed in Dictionary'
  210. !
  211.  
  212. remove: anObject ifAbsent: aBlock
  213.     self error: 'remove:ifAbsent: not allowed in Dictionary'
  214. !!
  215.  
  216.  
  217.  
  218. !Dictionary methodsFor: 'dictionary enumerating'!
  219. associationsDo: aBlock
  220.     super do: [ :assoc | aBlock value: assoc ]
  221. !
  222.  
  223. "These could be implemented more efficiently by doing the super do
  224.  directly, or doing the explicit scanning of the dictionary by hand"
  225. keysDo: aBlock
  226.     self associationsDo: [ :assoc | aBlock value: assoc key ]
  227. !
  228.  
  229. do: aBlock
  230.     self associationsDo: [ :assoc | aBlock value: assoc value ]
  231. !
  232.  
  233. collect: aBlock
  234.     | aBag |
  235.     aBag _ Bag new.
  236.     self do: [ :element | aBag add: (aBlock value: element) ].
  237.     ^aBag
  238. !
  239.  
  240. select: aBlock
  241.     | newDict |
  242.     newDict _ self species new.
  243.     self associationsDo:
  244.         [ :assoc | (aBlock value: assoc value)
  245.              ifTrue: [ newDict add: assoc ] ].
  246.     ^newDict
  247. !
  248.  
  249. reject: aBlock
  250.     self shouldNotImplement
  251. !
  252.  
  253. inject: value into: aBlock
  254.     self shouldNotImplement
  255. !!
  256.  
  257.  
  258.  
  259. !Dictionary methodsFor: 'misc math methods'!
  260.  
  261. = aDictionary
  262.     tally ~= aDictionary size ifTrue: [ ^false ].
  263.     self associationsDo:
  264.         [ :assoc | assoc value ~= (aDictionary at: assoc key
  265.                                            ifAbsent: [ ^false ])
  266.                      ifTrue: [ ^false ] ].
  267.     ^true
  268. !
  269.  
  270. hash
  271.     | hashValue |
  272.     hashValue _ tally.
  273.     self associationsDo:
  274.         [ :assoc | hashValue _ hashValue + assoc hash ].
  275.     ^hashValue
  276. !!
  277.  
  278.  
  279.  
  280. !Dictionary methodsFor: 'printing'!
  281.  
  282. printOn: aStream
  283.     aStream nextPutAll: self class name , ' (' .
  284.     self associationsDo:
  285.         [ :assoc | assoc key storeOn: aStream.
  286.                aStream nextPut: $,.
  287.            assoc value storeOn: aStream.
  288.            aStream nextPut: Character space ].
  289.     aStream nextPut: $)
  290. !!
  291.  
  292.  
  293.  
  294. !Dictionary methodsFor: 'storing'!
  295.  
  296. storeOn: aStream
  297.     | hasElements |
  298.     aStream nextPutAll: '(', self class name , ' new'.
  299.     hasElements _ false.
  300.     self associationsDo:
  301.         [ :assoc | aStream nextPutAll: ' at: '.
  302.                    assoc key storeOn: aStream.
  303.                aStream nextPutAll: ' put: '.
  304.            assoc value storeOn: aStream.
  305.            aStream nextPut: $;.
  306.            hasElements _ true ].
  307.     hasElements ifTrue: [ aStream nextPutAll: ' yourself' ].
  308.     aStream nextPut: $)
  309. !!
  310.  
  311.  
  312.  
  313. !Dictionary methodsFor: 'private methods'!
  314.  
  315. rehashObjectsAfter: index
  316.     "Rehashes all the objects in the collection after index to see if any of
  317.     them hash to index.  If so, that object is copied to index, and the
  318.     process repeats with that object's index, until a nil is encountered."
  319.     | i size count assoc |
  320.     i _ index.
  321.     size _ self basicSize.
  322.     count _ size.
  323.     [ count > 0 ]
  324.         whileTrue:
  325.         [ i _ i \\ size + 1.
  326.               assoc _ self basicAt: i.
  327.           assoc isNil ifTrue: [ ^self ].
  328.               ((assoc key hash \\ size) + 1) = index
  329.               ifTrue: [ self basicAt: index put: assoc.
  330.                   self basicAt: i put: nil.  "Be tidy"
  331.               index _ i ].
  332.               count _ count - 1 ]
  333. !
  334.  
  335. findKeyIndex: aKey ifFull: aBlock
  336.     "Tries to see if aKey exists as the key of an indexed variable (which is an
  337.     association).  If it's searched the entire dictionary and the key is 
  338.     not to be found, aBlock is evaluated and it's value is returned."
  339.     | index count size assoc |
  340.     size _ self basicSize.
  341.     index _ aKey hash \\ size + 1.
  342.     count _ size.
  343.     [ count > 0 ]
  344.         whileTrue:
  345.         [ assoc _ self basicAt: index.
  346.               (assoc isNil or: [ assoc key = aKey ])
  347.             ifTrue: [ ^index ].
  348.           index _ index \\ size + 1.
  349.           count _ count - 1. ].
  350.     ^aBlock value
  351. !
  352.         
  353. findKeyIndex: aKey
  354.     "Finds an association with the given key in the dictionary and returns its
  355.     index.  If the dictionary doesn't contain the object and there is no nil
  356.     element, the dictionary is grown and then the index of where the object
  357.     would go is returned."
  358.     ^self findKeyIndex: aKey
  359.            ifFull: [ self grow.
  360.                 self findKeyIndexNoGrow: aKey
  361.                   ifAbsent: [ ^self error: 'failed to grow a new empty element!!!' ] ]
  362. !
  363.  
  364. findKeyIndexNoGrow: aKey ifAbsent: aBlock
  365.     | index |
  366.     index _ self findKeyIndex: aKey ifFull: [ 0 ].
  367.     (index = 0 )
  368.         ifTrue: [ ^aBlock value ]
  369.     ifFalse: [ ^index ]
  370. !
  371.  
  372. grow
  373.     | newDict |
  374.     newDict _ self species new: self basicSize + self growSize.
  375.     self associationsDo: [ :assoc | newDict add: assoc ].
  376.     ^self become: newDict
  377. !
  378.  
  379. growSize
  380.     ^32
  381.  
  382. !!
  383.  
  384.